The String Widgets

  • HTMLWidget
  • LatexWidget
  • TextWidget
  • TextArea

These widgets are used to display data conventionally represented as strings.


In [ ]:
{-# LANGUAGE OverloadedStrings #-}
import IHaskell.Display.Widgets

In [ ]:
-- Constructors
html <- mkHTMLWidget
latex <- mkLatexWidget
text <- mkTextWidget
area <- mkTextArea

These widgets have a Text payload, represented by the StringValue field.

HTML and Latex

The HTMLWidget and LatexWidget display Text as rich formatted HTML and LaTeX respectively.


In [ ]:
-- Display the widgets
html
latex

In [ ]:
-- Set some html string
setField html StringValue "<b>Bold</b>"

In [ ]:
-- Set some latex string
setField latex StringValue "$x + y$"

-- The default width of LatexWidget is somewhat small
setField latex Width 400

We can also add some padding to the widgets.


In [ ]:
setField html Padding 10
setField latex Padding 10

TextWidget and TextArea

First, let's see what they look like:


In [ ]:
text
area

In [ ]:
-- Some padding
setField text Padding 5

The TextWidget and TextArea also have a Placeholder property, which represents the text displayed in empty widgets.


In [ ]:
setField text Placeholder "Enter your text here..."
setField area Placeholder "Parsed output will appear here..."

Both the widgets also accept input. The StringValue of the widget is automatically updated on every change to the widget. Additionally, the TextWidget also has a SubmitHandler which is triggered on hitting the return/enter key.

Below we set up the TextWidget and TextArea for parsing phone numbers using parsec. The TextWidget is used to recieve input, and the TextArea is used to display output.


In [ ]:
-- Import parsec and other required libraries

import Text.Parsec
import Text.Parsec.String
import Data.Text (pack, unpack)
import Control.Applicative ((<$>))

Now, we can write some parsers:


In [ ]:
-- Parse a single digit
digit :: Parser Char
digit = oneOf ['0'..'9']

-- Parse a multi-digit number.
number :: Parser Integer
number = do
  digits <- many1 digit -- At least one digit
  return (read digits)  -- Convert [Char] to Integer
  
-- Parse a country code, starting with a +.
countryCode :: Parser Integer
countryCode = do
  char '+'
  number
  
-- Parse an area code, optionally with parentheses.
areaCode :: Parser Integer
areaCode = choice [withParens, withoutParens]
  where
    withParens = between (char '(') (char ')') withoutParens
    withoutParens = number
  
-- Simple data type representing a phone number.
-- Real phone numbers are much more complex!
data PhoneNumber = PhoneNumber {
    phoneCountryCode :: Maybe Integer,
    phoneNumbers :: [Integer]
  } deriving (Eq, Show)
  
phoneNumber :: Parser PhoneNumber
phoneNumber = do
  -- Try to parse a country code. If it doesn't work, it's Nothing.
  c <- optionMaybe countryCode
  optional separator
  a1 <- areaCode
  separator -- Separator required after area code
  a2 <- number
  separator -- Separator required before last group of digits
  a3 <- number
  return (PhoneNumber c [a1, a2, a3])
  
  where
    separator = oneOf " -"

Now, we set the TextWidget's change handler to parse the input, and write the output to the TextArea.


In [ ]:
setField text ChangeHandler $ do
  input <- unpack <$> getField text StringValue
  str <- case parse phoneNumber "<text widget>" input of
             Left error -> return (show error)
             Right x -> return (show x)
  setField area StringValue (pack str)

The TextArea doesn't have a SubmitHandler, but does have a ChangeHandler. It is best used to display large amounts of text.

We can re-display the widgets (nobody likes to scroll needlessly):


In [ ]:
text
area